home *** CD-ROM | disk | FTP | other *** search
- {
- Pascal.i (of PCQ Pascal)
- Copyright (c) 1989 Patrick Quaid.
-
- These are the constants, types and variables required
- for the compiler.
-
- }
-
-
- CONST
-
- Hash_Size = 255; { Size of the Hash Table - 1 }
- literalsize = 8000; { room for character literals }
-
- eqsize = 127; { size of the error buffer }
-
- BufferSize = 2048; { size of Input buffer }
- BufferMax = BufferSize - 1; { Last index in Buffer }
-
- Spell_Max = 10000; { Size of the spelling records }
-
- MaxExprNodes = 255; { Pre-allocated nodes }
-
- MaxCode = 4096; { Last code position + 1 }
-
-
- {
- These are the symbols. Note that the first 40 or so
- correspond to the appropriate entries in the Reserved array.
- }
-
- TYPE
- Symbols = (and1, array1, begin1, by1, case1,
- const1, div1, do1, downto1, else1, end1, extern1,
- file1, for1, forward1, func1, goto1, if1, in1,
- label1, mod1, not1, of1, or1, packed1, private1,
- proc1, program1, record1, repeat1, return1, set1,
- shl1, shr1, then1, to1, type1, until1, var1, while1,
- with1, xor1,
-
- ident1, numeral1, asterisk1, becomes1, colon1,
- comma1, dotdot1, endtext1, equal1, greater1,
- leftbrack1, leftparent1, less1, minus1,
- notequal1, notgreater1, notless1, period1, plus1,
- rightbrack1, rightparent1, semicolon1, leftcurl1,
- rightcurl1, quote1, apostrophe1, carat1, at1, pound1,
- ampersand1, realdiv1, realnumeral1, unknown1, Char1,
- int2real, real2int, short2long, byte2short, byte2long,
- stanfunc1, field1);
-
- CONST
- LastReserved = Xor1;
-
- TYPE
-
- OpCodes = (op_ADD, op_ADDA, op_ADDQ, op_AND, op_ASL, op_ASR,
- op_BEQ, op_BGE, op_BGT, op_BLE, op_BLT,
- op_BNE, op_BPL, op_BRA, op_BSET, op_CLR,
- op_CMP, op_CNOP, op_DBRA, op_DC, op_DIVS,
- op_DS, op_END, op_EOR, op_EXG, op_EXT,
- op_JSR, op_LEA, op_LINK, op_LSL, op_LSR,
- op_MOVE, op_MOVEM, op_MOVEQ, op_MULS,
- op_NEG, op_NOT, op_OR, op_PEA, op_POP, op_PUSH,
- op_RESTORE, op_RTS, op_SAVE, op_SECTION, op_SEQ,
- op_SGE, op_SGT, op_SLE, op_SLT, op_SNE, op_SUB,
- op_SUBA, op_SUBQ, op_SWAP, op_TRAP, op_TST, op_UNLK,
- op_XDEF, op_XREF, op_None, op_LABEL, op_EOF);
-
-
- {_____e.g.___________extension__________}
-
- EAModes = ( ea_Constant, { #nnnn value of constant }
- ea_Absolute, { nnnn value of constant }
- ea_Literal, { #LitLab+nnnn offset into table }
- ea_Global, { _globalname address of ID }
- ea_Address, { #_globalname address of ID }
- ea_Index, { d16(An) offset value }
- ea_String, { "_p%acos" address of string }
- ea_Label, { _p%nnn label number }
- ea_RegInd, { d8(An,Dm.l) d8 shl 8 or Dm }
- ea_RegList, { Rn/Rm/... Mask of registers 0..15 }
- ea_Offset, { #_global+nnn ID pointer, then offset }
- ea_Indirect, { (An) none }
- ea_PostInc, { (An)+ none }
- ea_PreDec, { -(An) none }
- ea_Register, { Rn none }
- ea_None { not used none }
- );
-
- TypeObject = (ob_array, ob_set, ob_record, ob_ordinal, ob_pointer,
- ob_enumer, ob_subrange, ob_synonym, ob_file, ob_real);
-
- TypeRec = Record
- Next : ^TypeRec;
- Object : TypeObject;
- SubType : ^TypeRec;
- Ref : Address; { An IDPtr to record fields, or
- a TypePtr to the index type of an array }
- Upper,
- Lower : Integer;
- Size : Integer;
- end;
- TypePtr = ^TypeRec;
-
- IDObject = (global, local, refarg, valarg, proc, func, obtype, field,
- stanproc, stanfunc, constant, pending_type, typed_const,
- lab);
-
- IDStorage = (st_none, st_external, st_internal, st_private, st_initialized,
- st_forward);
-
- IDRec = Record
- Next : ^IDRec;
- Name : String;
- Object : IDObject;
- VType : TypePtr;
- Param : ^IDRec;
- Level : Short;
- Storage : IDStorage;
- Offset : Integer;
- Unique : Integer;
- end;
- IDPtr = ^IDRec;
-
- BlockRec = Record
- Previous : ^BlockRec;
- FirstType: TypePtr;
- Level : Short;
- Table : Array [0..Hash_Size] of IDPtr;
- end;
- BlockPtr = ^BlockRec;
-
- { The expression types. The first one declares the normal expression
- node, and is used extensively throughout Expression.p and Generate.p.
- The second is just an enumeration of the register names, which is
- used mainly in Generate.p. }
-
- ExprNode = record
- Kind : Symbols; { operator, var1, type1, etc. }
- Used : Boolean; { currently allocated }
- Next, { list of parameter expressions }
- Left, { Left expression, or only if unary op }
- Right : ^ExprNode; { Right side of expression }
- EType : TypePtr; { Result type of the expression }
- Value : Integer; { constant value or ID Ptr }
- end;
- ExprPtr = ^ExprNode;
-
- Regs = (d0,d1,d2,d3,d4,d5,d6,d7,a0,a1,a2,a3,a4,a5,a6,a7);
-
- RegName = Array [0..1] of Char;
-
- { The following record allows me to nest include calls to the
- limits of memory. }
-
- FileRec = Record
- PCQFile : Text;
- Previous: ^FileRec;
- SaveLine,
- SaveStart : Integer;
- SaveChar : Char;
- Name : String;
- end;
- FileRecPtr = ^FileRec;
-
- { The next record saves the names of include files so I won't load
- them twice. Note that only as much of the record as is required
- for a particular file name is allocated. }
-
- IncludeRec = record
- Next : ^IncludeRec;
- Name : Array [0..100] of Char;
- end;
- IncludeRecPtr = ^IncludeRec;
-
- { This next record helps implement the With statement. For each active
- with statement, there is a corresponding record. These are stacked
- (to handle scoping), and simply contain a pointer to the proper type. }
-
- WithRec = Record
- Previous : ^WithRec;
- RecType : TypePtr;
- Offset : Integer;
- end;
- WithRecPtr = ^WithRec;
-
- { This is the spelling table stuff. Originally I was allocating
- memory for ID names one at a time, then freeing them at the end of
- a procedure definition. I was probably wasting too much time allocating
- memory, however, so I switched back to a one-big-array method, although
- this is somewhat more flexible than the 1.0 version. }
-
- SpellRec = Record
- Previous : ^SpellRec;
- First : Integer; { The first index held in this record }
- Data : Array [0..Spell_Max] of Char;
- end;
- SpellRecPtr = ^SpellRec;
-
- CONST
- RN : Array [d0..a7] of RegName = ( 'd0','d1','d2','d3',
- 'd4','d5','d6','d7',
- 'a0','a1','a2','a3',
- 'a4','a5','a6','sp');
-
- Extensions : Array [ea_Constant..ea_None] of Byte =
- (1,1,1,1,1,1,1,1,1,1,2,0,0,0,0,0);
-
- OpText : Array [op_ADD..op_LABEL] of String = (
- "add", "adda", "addq", "and", "asl", "asr",
- "beq", "bge", "bgt", "ble", "blt",
- "bne", "bpl", "bra", "bset", "clr",
- "cmp", "cnop", "dbra", "dc", "divs",
- "ds", "end", "eor", "exg", "ext",
- "jsr", "lea", "link", "lsl", "lsr",
- "move", "movem", "moveq", "muls",
- "neg", "not", "or", "pea", "pop", "push",
- "restore", "rts", "save", "section", "seq",
- "sge", "sgt", "sle", "slt", "sne", "sub",
- "suba", "subq", "swap", "trap", "tst", "unlk",
- "xdef", "xref", "none", "Label");
-
-
- VAR
-
- {
- These are the global variables for the compiler.
- When this file is included by the main program, space is
- allocated for the variables. The external files, although
- they also import this file, just generate external
- references.
- }
-
- CurrentBlock : BlockPtr;
-
- { Space for literal strings and arrays in the program text }
-
- LitQ : Array [0..LiteralSize] of Char;
- LitPtr : Integer;
-
- { The reserved words, held here in order to make searching quicker }
-
- Reserved : Array [And1..LastReserved] of String;
-
- { These four implement the error queue, which prints out the latest
- 128 chars or two lines, whichever is less, when an error occurs }
-
- ErrorQ : Array [0..EQSize] of Char;
- EQStart : Short;
- EQEnd : Short;
- ErrorPtr : Short;
-
- { The spelling table variables }
-
- CurrentSpellRec : SpellRecPtr;
- SpellPtr : Integer;
-
- { The With variables }
-
- FirstWith,
- LastWith : WithRecPtr;
- StackLoad : Integer;
-
- { Expression evaluation variables }
-
- UsedRegs : Integer; { Bit map of registers in use }
-
- MathLoaded : Boolean; { Is FP math library address in a6? }
-
- { Register allocation counters }
-
- NextDataRegister : Regs;
- NextAddressRegister : Regs;
-
- { Expression node management }
-
- ExpressionNodeStore : Array [0..MaxExprNodes] of ExprNode;
- NextFreeExprNode : Integer;
-
- { Code table management }
-
- Code_Table : ^Array [0..MaxInt] of Integer;
- { Table of coded instructions }
- NextCode : Integer; { Position in Code_Table for next }
-
-
- StandardStorage : IDStorage; { The default storage mode }
- NxtLab : Integer; { Just the current label }
- LitLab : Integer; { Label of the literals }
- StackSpace : Integer; { Counts local var stack space }
- ErrorCount : Integer; { Literally the # of errors }
- InFile : FileRecPtr; { The current input record }
- OutFile : Text; { The main assembly output }
- MainMode : Boolean; { Is this a program file? }
- IncludeList : IncludeRecPtr;{ list of include files }
- FnStart : Integer; { The line # of the start of this }
- LineNo : Integer; { Current line number. }
-
- CurrFn : IDPtr; { Index of current proc or func }
- BadType, { Universal type index }
- IntType, { These are just pointers to }
- BoolType, { the appropriate types }
- RealType,
- CharType,
- TextType,
- StringType,
- AddressType,
- ShortType,
- ByteType,
- LiteralType : TypePtr; { Temp type for array lits }
- CurrSym : Symbols; { Current symbol }
- SymLoc : Integer; { Literal integer }
- RealValue : Real; { Literal float }
- SymText : String; { Holds ident. text }
- CurrentChar : Char; { The current char! }
- BuffedChar : Char; { Buffered character }
- CharBuffed : Boolean; { is a char buffered? }
- RangeCheck : Boolean; { Doing rangechecks? }
- IOCheck : Boolean; { Doing IO checks? }
- Inform : Boolean; { Verbose updates? }
- DoReport : Boolean; { Reporting Expr Trees }
- ShortCircuit : Boolean; { Do short circuit evaluations }
- SmallInitialize : Boolean; { Link in small initialize code }
- StdOut_Interactive : Boolean; { stdout is a console }
- ConstantExpression : Boolean; { True => Typed constants become constants }
- MainName : String; { Main file name }
- OutName : String; { The output file name }
- TypeID : IDPtr; { Points to a type's ID rec }
-